TableReadTitle Function

private function TableReadTitle(lines) result(title)

Read the title of the table. Title is optional. Arguments: lines collections of lines Result: Return title if exists

Arguments

Type IntentOptional Attributes Name
character(len=LINELENGTH), intent(in), POINTER :: lines(:)

Return Value character(len=300)


Variables

Type Visibility Attributes Name Initial
character(len=300), public :: before
integer(kind=short), public :: i
integer(kind=short), public :: ios
character(len=LINELENGTH), public :: string
logical, public :: titleFound

Source Code

FUNCTION TableReadTitle &
  ( lines )               &
RESULT (title)

! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringCompact, StringToUpper, StringSplit

IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = LINELENGTH), INTENT (IN), POINTER :: lines (:)

! Local scalars:
CHARACTER (LEN = 300)  :: title 
INTEGER (KIND = short) :: ios
INTEGER (KIND = short) :: i
CHARACTER (LEN = LINELENGTH)  :: string
CHARACTER (LEN = 300)  :: before
LOGICAL                :: titleFound            
!------------end of declaration------------------------------------------------

string = ''
titleFound = .FALSE.

! scan table 
DO i = 1, SIZE (lines)
  string =  lines (i)
  CALL StringSplit ( ':', string, before)
  
  IF (  StringToUpper ( before(1:5)) == "TITLE" ) THEN !found title
    CALL StringSplit ( '#', string, before) !remove inline comment
    title = before
    titleFound = .TRUE.
    RETURN
  END IF
END DO

IF ( .NOT. titleFound ) THEN
  title = ''
  !Title is not mandatory element of a table.
END IF
END FUNCTION TableReadTitle